home *** CD-ROM | disk | FTP | other *** search
- INCLUDE TITLE.MAC
- .TITLE <COM_PKG -- COMn: Routines for Lattice C>
- .SBTTL <History and Copyright Notice>
-
- ; com_pkg.asm 1 Dec 83 Craig Milo Rogers at USC/ISI
- ; Corrected a few typos. Added Deficiencies section.
- ; Clear interrupt controller before polling UART.
- ; com_pkg.asm 20 Nov 83 Craig Milo Rogers at USC/ISI
- ; Use int_pkg routines to set/restore interrupt vectors.
- ; com_pkg.asm 15 Nov 83 Craig Milo Rogers at USC/ISI
- ; Converted to PDP-11-style TITLEs.
- ; Converted control info to a STRUC.
- ; com_pkg.asm 10 Nov 83 Craig Milo Rogers at USC/ISI
- ; Bug fixes in initialization code.
- ; com_pkg.asm 30 Oct 83 Craig Milo Rogers at USC/ISI
- ; Support COM1: and COM2:.
- ; com_pkg.asm 28 Oct 83 Craig Milo Rogers at USC/ISI
- ; Modified to take transmit and receive buffer addresses and
- ; lengths as initialization arguments.
- ; com_pkg.asm 26 Oct 83 Craig Milo Rogers at USC/ISI
- ; These routines provide an interrupt-driven circular buffer
- ; interface to the COM1: device. This version interfaces with the
- ; multi-model Lattice C compiler version 1.05. Earlier history:
- ;
- ; COM_PKG1 provides a library of serial port routines
- ; Adapted from code by John Romkey and Jerry Saltzer of MIT
- ; by Richard Gillmann (GILLMANN@ISIB), 1983
- ;
-
- .SBHED Overview
-
- ; This is a module of routines for interfacing with the
- ; COM1: communications interface on the IBM PC. The code has
- ; been carefully constructed to properly drive the 8250 UART
- ; and the 8259 Interrupt Controller. External circular buffers
- ; are used for transmit and receive.
-
- ; Entry points (Lattice C 1.05 calling conventions):
-
- ; void
- ; com_ini(unit, divisor, tbuf, tbuflen, rbuf, rbuflen)
- ; /* Initializes port and interrupt vector. */
- ; int unit; /* 1 ==> COM1:, 2 ==> COM2:. */
- ; int divisor; /* Baud rate generator divisor. */
- ; char *tbuf; /* Transmit buffer address. */
- ; int tbuflen; /* Transmit buffer length. */
- ; char *rbuf; /* Receive buffer address. */
- ; int rbuflen; /* Receive buffer length. */
-
- ; void
- ; com_trm(unit) /* Turns off interrupts from the aux port. */
- ; int unit; /* 1 ==> COM1:, 2 ==> COM2:. */
-
- ; void
- ; com_doff(unit) /* Turns off DTR. */
- ; int unit; /* 1 ==> COM1:, 2 ==> COM2:. */
-
- ; void
- ; com_don(unit) /* Turns on DTR. */
- ; int unit; /* 1 ==> COM1:, 2 ==> COM2:. */
-
- ; int /* Number of characters in input buffer. */
- ; com_icnt(unit) /* Returns number of characters in input buffer. */
- ; int unit; /* 1 ==> COM1:, 2 ==> COM2:. */
-
- ; int /* Next character in input buffer or EOF. */
- ; com_getc(unit) /* Reads next character in input buffer. */
- ; int unit; /* 1 ==> COM1:, 2 ==> COM2:. */
-
- ; int /* Number of free bytes in output buffer. */
- ; com_ocnt(unit) /* Returns number of free bytes in output buffer. */
- ; int unit; /* 1 ==> COM1:, 2 ==> COM2:. */
-
- ; bool /* Returns FALSE if no more room. */
- ; com_putc(unit, ch) /* Writes a character to the output buffer. */
- ; int unit; /* 1 ==> COM1:, 2 ==> COM2:. */
- ; char ch; /* The character to write. */
-
- ; bool /* Returns FALSE if no more room. */
- ; com_loopc(unit, ch) /* Writes a character to the input buffer. */
- ; int unit; /* 1 ==> COM1:, 2 ==> COM2:. */
- ; char ch; /* The character to write. */
-
- ; void
- ; com_bon(unit) /* Turns on BREAK. */
- ; int unit; /* 1 ==> COM1:, 2 ==> COM2:. */
-
- ; void
- ; com_boff(unit) /* Turns off BREAK. */
- ; int unit; /* 1 ==> COM1:, 2 ==> COM2:. */
-
- ; void
- ; com_break(unit) /* Sends complete BREAK sequence. */
- ; int unit; /* 1 ==> COM1:, 2 ==> COM2:. */
-
- .SBHED Deficiencies
-
- ; 1) The initialization routine should pre-calculate the 8250
- ; addresses, and store them in the control block. This will
- ; save a few percent of code space, and speed up the interrupt
- ; service routine.
-
- ; 2) There should be a puts() routine to optimize the common case
- ; of transmitting a buffer of characters. A gets() routine
- ; would be desirable for symmetry, although the time savings is
- ; less likely to be significant.
-
- ; 3) There should be finer control over the UART initialization.
- ; It might also be nice to be able to change UART parameters
- ; dynamically.
-
- ; 4) There should be a way to respond to modem control signals,
- ; such as Ring Indicator, and to generate modem control signals
- ; besides DTR.
-
- ; 5) The com_break() routine has it's name truncated. This should be
- ; repaired when C supports long names. The int_setup()
- ; external, etc. are also affected.
-
- ; 6) There should be provision for addional COM units.
-
- ; 7) The COM register base addresses should be obtained from the BIOS.
-
- ; 8) It should be possible for COM units to share an interrupt level.
-
- ; 9) The error returns from int_setup() and int_restore() should be
- ; checked.
-
- ; 10) Perhaps the initialization code can be rewritten so interrupts
- ; don't have to be disabled for quite so long.
-
- .SBHED Declarations
-
- IF1
- INCLUDE DOS.MAC ; C segments.
- INCLUDE BMAC.MAC ; C calling conventions.
- ENDIF
-
- ; int_pkg routines:
- BEXTRN INT_SETU ; Setup an interrupt vector.
- BEXTRN INT_REST ; Restore an interrupt vector.
-
- ; COM1: parameters:
- COM1_INT EQU 4 ; Interrupt number for comm. port.
- COM1_BASE EQU 3F8H ; Base address of 8250 registers.
-
- ; COM2: parameters:
- COM2_INT EQU 3 ; Interrupt number for comm. port.
- COM2_BASE EQU 2F8H ; Base address of 8250 registers.
-
-
- INT_OFF EQU 08H ; Converts 8259 interrupt numbers to
- ; 8088 interrupt numbers.
-
- ; 8250 device registers:
- DATREG EQU 0H ; Data register.
- DLL EQU 0H ; Low divisor latch.
- DLH EQU 1H ; High divisor latch.
- IER EQU 1H ; Interrupt enable register.
- IIR EQU 2H ; Interrupt identification register.
- LCR EQU 3H ; Line control register.
- MCR EQU 4H ; Modem control register.
- LSR EQU 5H ; Line status register.
- MSR EQU 6H ; Modem status register.
-
- DLA EQU 80H ; Divisor latch access.
- MODE EQU 03H ; 8-bits, no parity.
- DTR EQU 0BH ; Bits to set dtr line.
- DTR_OF EQU 00H ; Turn off dtr, rts, and the interupt driver.
- THRE EQU 20H ; Mask to find status of xmit holding reg.
- RXINT EQU 01H ; Enable data available interrupt.
- TXINT EQU 02H ; Enable tx holding register empty interrupt.
- TCHECK EQU 20H ; Mask for checking tx reg stat on interrupt.
- RCHECK EQU 01H ; Mask for checking rx reg stat on interrupt.
- INT_PEND EQU 01H ; There is an interrupt pending.
- MSTAT EQU 00H ; Modem status interrupt.
- WR EQU 02H ; Ready to xmit data.
- RD EQU 04H ; Received data interrupt.
- LSTAT EQU 06H ; Line status interrupt.
- ACK EQU 244 ; Acknowledge symbol.
- PARITY EQU 7FH ; Bits to mask off parity.
- BREAK EQU 40H ; Bits to cause break.
-
- ; 8259 Interrupt Controller:
- IMR EQU 21H ; Interrupt mask register.
- OCW2 EQU 20H ; Operational control word on 8259.
- EOI EQU 60H ; Specific end of interrupt.
-
- ; C return values:
- TRUE EQU 1 ; Truth.
- FALSE EQU 0 ; Falsehood.
-
-
- COMX_CTRL STRUC ; Control parameters for COMn:
-
- TBUF_SEG DW ? ; Transmit buffer segment number.
- TBUF_OFF DW ? ; Transmit buffer offset.
- TBUF_SIZE DW ? ; Transmit buffer size.
-
- START_TDATA DW ? ; Index to first character in x-mit buffer.
- END_TDATA DW ? ; Index to first free space in x-mit buffer.
- SIZE_TDATA DW ? ; Number of characters in x-mit buffer.
-
- RBUF_SEG DW ? ; Receive buffer segment number.
- RBUF_OFF DW ? ; Receive buffer offset.
- RBUF_SIZE DW ? ; Receive buffer size.
-
- START_RDATA DW ? ; Index to first character in rec. buffer.
- END_RDATA DW ? ; Index to first free space in rec. buffer.
- SIZE_RDATA DW ? ; Number of characters in rec. buffer.
-
- COMX_INT DW ? ; Interrupt number for comm. port.
- COMX_BASE DW ? ; I/O base address of 8250 registers.
-
- COMX_CTRL ENDS ; End of the structure definition.
-
- .SBHED <Data Storage>
-
- DSEG
- COM1_CTRL COMX_CTRL <> ; Control parameters for COM1:.
- COM2_CTRL COMX_CTRL <> ; Control parameters for COM2:.
- ENDDS
-
- PSEG ; All the rest is code.
-
- .SBHED <COM1: and COM2: Specific Interrupt Handlers>
- ;
- ; DATASEG - DS for Use by Interrupt Handler
- ;
- ; WARNING!
- ; Note the impure use of DATASEG below. This code is not ROMmable.
- ;
- DATASEG DW 0 ; Holds our data segment number.
-
- ;
- ; INT_HNDLR1 - Handles Interrupts Generated by COM1:
- ;
- INT_HNDLR1 PROC FAR ;;; Enter here on interrupt.
- PUSH SI ;;; Save old source index.
- MOV SI,OFFSET COM1_CTRL ;;; Get pointer to control block.
-
- JMP SHORT INT_COMMON ;;; Go join common interrupt handler.
-
-
- ;
- ; INT_HNDLR2 - Handles Interrupts Generated by COM2:
- ;
- INT_HNDLR2 PROC FAR ;;; Enter here on interrupt.
- PUSH SI ;;; Save old source index.
- MOV SI,OFFSET COM2_CTRL ;;; Get pointer to control block.
- ;;; Fall into common interrupt handler:
-
- .SBHED <Common Interrupt Handler>
-
- INT_COMMON:
- PUSH DS ;;; Save data segment register.
- PUSH CS:DATASEG ;;; Set up new data segment.
- POP DS ;;;
- PUSH ES ;;; Save previous context on existing stack.
- PUSH BP ;;;
- PUSH DI ;;;
- PUSH AX ;;;
- PUSH BX ;;;
- PUSH CX ;;;
- PUSH DX ;;;
-
- ;;; Clear the interrupt controller flag before polling interrupt sources
- ;;; on the UART to avoid losing additional COM interrupts.
-
- MOV DX,OCW2 ;;; Tell the 8259 that I'm done.
- MOV AL,EOI ;;; Get the End-of-Interrupt code.
- OR AL,BYTE PTR [SI].COMX_INT ;;; Set to specific int. number.
- OUT DX,AL ;;;
-
- ;;; Find out where interrupt came from and jump to routine to handle it:
- MOV DX,[SI].COMX_BASE ;;;
- ADD DX,IIR ;;;
- IN AL,DX ;;;
- CMP AL,RD ;;;
- JZ RX_INT ;;; If it's from the receiver.
- CMP AL,WR ;;;
- JZ TX_INT ;;; If it's from the transmitter.
- CMP AL,LSTAT ;;;
- JZ LSTAT_INT ;;; Interrupt becuase of line status.
- CMP AL,MSTAT ;;;
- JZ MSTAT_INT ;;; Interrupt because of modem status.
- JMP FAR PTR INT_END ;;; Interrupt when no int. pending, go away.
-
- LSTAT_INT:
- MOV DX,[SI].COMX_BASE ;;;
- ADD DX,LSR ;;; Clear interrupt.
- IN AL,DX ;;;
- JMP REPOLL ;;; See if any more interrupts.
-
- MSTAT_INT:
- MOV DX,[SI].COMX_BASE ;;;
- ADD DX,MSR ;;; Clear interrupt.
- IN AL,DX ;;;
- JMP REPOLL ;;; See if any more interrupts.
-
- TX_INT:
- MOV DX,[SI].COMX_BASE ;;;
- ADD DX,LSR ;;;
- IN AL,DX ;;;
- AND AL,TCHECK ;;;
- JNZ GOODTX ;;; Good interrupt.
- JMP REPOLL ;;; See if any more interrupts.
-
- GOODTX: CMP [SI].SIZE_TDATA,0 ;;; See if any more data to send.
- JNE HAVE_DATA ;;; If not equal then data to send.
-
- ;;; If no data to send then reset tx interrupt and return.
- MOV DX,[SI].COMX_BASE ;;;
- ADD DX,IER ;;;
- MOV AL,RXINT ;;;
- OUT DX,AL ;;;
- JMP REPOLL ;;;
-
- HAVE_DATA:
- MOV ES,[SI].TBUF_SEG ;;; Get transmit buffer segment num.
- MOV DI,[SI].TBUF_OFF ;;; Get transmit buffer offset.
- MOV BX,[SI].START_TDATA ;;; BX points to next char to be sent.
- MOV DX,[SI].COMX_BASE ;;;
- ADD DX,DATREG ;;; DX equals port to send data to.
- MOV AL,ES:[BX+DI] ;;; Get data from buffer.
- OUT DX,AL ;;; Send data.
- INC BX ;;; Increment START_TDATA.
- CMP BX,[SI].TBUF_SIZE ;;; See if gone past end.
- JB NTADJ ;;; If not then skip.
- XOR BX,BX ;;; Reset to beginning.
- NTADJ: MOV [SI].START_TDATA,BX ;;; Save START_TDATA.
- DEC [SI].SIZE_TDATA ;;; One less character in xmit buffer.
- JMP REPOLL ;;;
-
- RX_INT:
- MOV DX,[SI].COMX_BASE ;;;
- ADD DX,LSR ;;; Check and see if read is real.
- IN AL,DX ;;;
- AND AL,RCHECK ;;; Look at receive data bit.
- JNZ GOOD_RX ;;; Real, go get byte.
- JMP REPOLL ;;; Go look for other interrupts.
-
- GOOD_RX:
- MOV DX,[SI].COMX_BASE ;;;
- ADD DX,DATREG ;;;
- IN AL,DX ;;; Get data.
- MOV DX,[SI].RBUF_SIZE ;;; Get size of buffer.
- CMP [SI].SIZE_RDATA,DX ;;; See if any room for data.
- JAE REPOLL ;;; If no room then look for more interrupts.
- MOV ES,[SI].RBUF_SEG ;;; Get receive buffer segment number.
- MOV DI,[SI].RBUF_OFF ;;; Get receive buffer offset.
- MOV BX,[SI].END_RDATA ;;; BX points to free space.
- MOV ES:[BX+DI],AL ;;; Send data to buffer.
- INC [SI].SIZE_RDATA ;;; Got one more character.
- INC BX ;;; Increment END_RDATA pointer.
- CMP BX,DX ;;; See if gone past end.
- JB NRADJ ;;; If not then skip,
- XOR BX,BX ;;; else adjust to beginning.
- NRADJ: MOV [SI].END_RDATA,BX ;;; Save value.
-
- REPOLL:
- MOV DX,[SI].COMX_BASE ;;; Read the line status register.
- ADD DX,LSR ;;; We always expect receive data, so
- IN AL,DX ;;; check status to see if any is ready.
- MOV BL,AL ;;; Save for transmit check, below.
- AND AL,RCHECK ;;; Get received data bit.
- JNZ GOOD_RX ;;; Yes, go accept the byte.
-
- ADD DX,(IER-LSR) ;;; Look at transmit condition
- IN AL,DX ;;; to see if we are enabled to send data.
- AND AL,TXINT ;;;
- JZ INT_END ;;; Not enabled, so go away.
- AND BL,TCHECK ;;; Check saved status for xmit done.
- JZ INT_END ;;;
- JMP GOODTX ;;; Transmitter is finished, go get more data.
-
- INT_END:
- POP DX ;;; Restore previous context.
- POP CX ;;;
- POP BX ;;;
- POP AX ;;;
- POP DI ;;;
- POP BP ;;;
- POP ES ;;;
- POP DS ;;;
- POP SI ;;;
- IRET ;;; Return from interrupt.
-
- INT_HNDLR2 ENDP
- INT_HNDLR1 ENDP
-
- .SBHED <SET_SI -- Select COM Control Block>
-
- ; This internal routine is called to point to the
- ; appropriate control block.
- ;
- ; Calling sequence:
- ; MOV AX,UNIT
- ; CALL SET_SI
-
- SET_SI PROC NEAR
- CMP AX,1 ; Is this for unit 1?
- JNE SET_CTRL2 ; (must be for unit 2)
-
- MOV SI,OFFSET COM1_CTRL ; Point to COM1: control area.
- RET ; Return to caller.
-
- SET_CTRL2:
- MOV SI,OFFSET COM2_CTRL ; Point to COM2: control area.
- RET ; Return to caller.
-
- SET_SI ENDP
-
- .SBHED <COM_INI -- Initialize Communication Port>
-
- ; void
- ; com_ini(unit, divisor, tbuf, tbuflen, rbuf, rbuflen)
- ; /* Initializes port and interrupt vector. */
- ; int unit; /* 1 ==> COM1:, 2 ==> COM2:. */
- ; int divisor; /* Baud rate generator divisor. */
- ; char *tbuf; /* Transmit buffer address. */
- ; int tbuflen; /* Transmit buffer length. */
- ; char *rbuf; /* Receive buffer address. */
- ; int rbuflen; /* Receive buffer length. */
-
- ; Initialize the Intel 8250 and set up interrupt vector to int_hndlr.
-
- IF LDATA
- BENTRY COM_INI <UNIT,DIVISOR,TBOFF,TBSEG,TBLEN,RBOFF,RBSEG,RBLEN>
- ELSE
- BENTRY COM_INI <UNIT,DIVISOR,TBOFF,TBLEN,RBOFF,RBLEN>
- ENDIF
- AUTO <HANDLR>
-
- MOV AX,UNIT ; Get the unit number.
- CALL SET_SI ; Point to proper control area.
- ; (Leaves AX unchanged)
- CMP AX,2 ; Initializing unit #2?
- JE INIT2 ; (yes)
-
- ; Select constants for unit #1:
- MOV AX,COM1_INT ; Interrupt number.
- MOV BX,COM1_BASE ; I/O base address.
- MOV CX,OFFSET INT_HNDLR1 ; Start of interrupt handler.
-
- JMP SHORT INITCOM ; Go join common code.
-
- INIT2: ; Select constants for unit #2:
- MOV AX,COM2_INT ; Interrupt number.
- MOV BX,COM2_BASE ; I/O base address.
- MOV CX,OFFSET INT_HNDLR2 ; Start of interrupt handler.
- ; Fall into INITCOM:
-
- INITCOM:
- MOV [SI].COMX_INT,AX ; Save the interrupt number.
- MOV [SI].COMX_BASE,BX ; Save the I/O base address.
- MOV HANDLR,CX ; Save the interrupt handler starting address.
-
- MOV AX,DS ; Copy our data segment number.
- IFE LDATA
- MOV ES,AX ; Save for buffer addresses.
- ENDIF
- MOV CS:DATASEG,AX ; Store segment # in code space (gulp!).
-
- IF LDATA
- MOV AX,TBSEG ; Get the transmit buffer segment number.
- ENDIF
- MOV [SI].TBUF_SEG,AX ; Save it.
- MOV BX,TBOFF ; Copy the transmit buffer offset.
- MOV [SI].TBUF_OFF,BX ;
- MOV BX,TBLEN ; Copy the transmit buffer length.
- MOV [SI].TBUF_SIZE,BX ;
-
- IF LDATA
- MOV AX,RBSEG ; Get the receive buffer segment number.
- ENDIF
- MOV [SI].RBUF_SEG,AX ; Save it.
- MOV AX,RBOFF ; Copy the receive buffer offset.
- MOV [SI].RBUF_OFF,AX ;
- MOV AX,RBLEN ; Copy the receive buffer length.
- MOV [SI].RBUF_SIZE,AX ;
-
- XOR AX,AX ; Clear the accumulator.
- MOV [SI].START_TDATA,AX ; Reset start of transmitted data.
- MOV [SI].END_TDATA,AX ; Reset end of transmitted data.
- MOV [SI].SIZE_TDATA,AX ; Reset number of transmitted chars.
-
- MOV [SI].START_RDATA,AX ; Reset start of received data.
- MOV [SI].END_RDATA,AX ; Reset end of received data.
- MOV [SI].SIZE_RDATA,AX ; Reset number of received chars.
-
- CLI ; ******* Disable Interrupts *******
-
- MOV DX,[SI].COMX_BASE ;;;
- ADD DX,MCR ;;; Reset the UART (AX is still zero).
- OUT DX,AL ;;;
-
- ADD DX,(LSR-MCR) ;;; Reset line status condition.
- IN AL,DX ;;;
- ADD DX,(DATREG-LSR) ;;; Reset receive data condition.
- IN AL,DX ;;;
- ADD DX,(MSR-DATREG) ;;; Reset modem deltas and conditions.
- IN AL,DX ;;;
-
- ADD DX,(LCR-MSR) ;;; Set baud rate with the passed argument.
- MOV AL,DLA+MODE ;;;
- OUT DX,AL ;;;
- ADD DX,(DLL-LCR) ;;;
- MOV AX,DIVISOR ;;;
- OUT DX,AL ;;; Low byte of passed argument.
- ADD DX,(DLH-DLL) ;;;
- MOV AL,AH ;;;
- OUT DX,AL ;;; High byte of passed argument.
-
- ADD DX,(LCR-DLH) ;;; Set 8250 to 8 bits, no parity.
- MOV AL,MODE ;;;
- OUT DX,AL ;;;
-
- PUSH SI ;;; Save pointer to COM block.
- MOV AX,[SI].COMX_INT ;;; Get the 8259 interrupt number.
- ADD AX,INT_OFF ;;; Convert to 8086 interrupt number.
- BCALL INT_SETU <AX HANDLR CS> ;;; Call int_setup(vec, newip, newcs).
- POP SI ;;; Restore data block pointer.
-
- ;;; Enable interrupts on 8259 and 8250:
- IN AL,IMR ;;; Get current enable bits on 8259.
- MOV CL,BYTE PTR [SI].COMX_INT ;;; Get interrupt number.
- MOV BL,1 ;;; Convert to
- SHL BL,CL ;;; bit position.
- NOT BL ;;; Clear current
- AND AL,BL ;;; interrupt bit.
- OUT IMR,AL ;;; Set enable on 8259.
- MOV DX,[SI].COMX_BASE ;;;
- ADD DX,IER ;;; Enable interrupts on 8250.
- MOV AL,RXINT ;;;
- OUT DX,AL ;;;
- ADD DX,(MCR-IER) ;;; Set dtr and enable int driver.
- MOV AL,DTR ;;;
- OUT DX,AL ;;;
-
- STI ;;; ******* Enable Interrupts *******
- ;;; (Next instruction still disabled)
- BEND COM_INI
-
- .SBHED <COM_TRM -- Turn Off Interrupts and Shutdown>
-
- ; void
- ; com_trm(unit) /* Turns off interrupts from the COM1: port. */
- ; int unit; /* 1 ==> COM1:, 2 ==> COM2:. */
-
- BENTRY COM_TRM <UNIT>
-
- MOV AX,UNIT ; Point to COM1: or COM2: save area.
- CALL SET_SI ;
-
- MOV DX,[SI].COMX_BASE
- ADD DX,IER ; Turn off 8250.
- MOV AL,0
- OUT DX,AL
-
- IN AL,IMR ; Turn off 8259.
- MOV CL,BYTE PTR [SI].COMX_INT ; Get interrupt number.
- MOV BL,1 ; Convert to
- SHL BL,CL ; bit position.
- OR AL,BL ; Disable this interrupt.
- OUT IMR,AL
-
- ; Reset interrupt vector:
- MOV AX,[SI].COMX_INT ; Get the 8259 interrupt number.
- ADD AX,INT_OFF ; Convert to 8086 interrupt number.
- BCALL INT_REST <AX> ; Call int_restore(vec).
-
- BEND COM_TRM
-
- .SBHED <COM_DOFF -- Turn off DTR>
-
- ; void
- ; com_doff(unit) /* Turns off DTR. */
- ; int unit; /* 1 ==> COM1:, 2 ==> COM2:. */
-
- ; Turns off DTR to tell modems that the terminal has gone away
- ; and to hang up the phone.
-
- BENTRY COM_DOFF <UNIT>
-
- MOV AX,UNIT ; Point to COM1: or COM2: save area.
- CALL SET_SI ;
-
- MOV DX,[SI].COMX_BASE
- ADD DX,MCR
- MOV AL,DTR_OF
- OUT DX,AL
-
- BEND COM_DOFF
-
- .SBHED <COM_DON -- Turn On DTR>
-
- ; void
- ; com_don(unit) /* Turns on DTR. */
- ; int unit; /* 1 ==> COM1:, 2 ==> COM2:. */
-
- BENTRY COM_DON <UNIT>
-
- MOV AX,UNIT ; Point to COM1: or COM2: save area.
- CALL SET_SI ;
-
- MOV DX,[SI].COMX_BASE
- ADD DX,MCR
- MOV AL,DTR
- OUT DX,AL
-
- BEND COM_DON
-
- .SBHED <COM_ICNT -- Return Number of Input Bytes>
-
- ; int /* Number of characters in input buffer. */
- ; com_icnt(unit) /* Returns number of characters in input buffer. */
- ; int unit; /* 1 ==> COM1:, 2 ==> COM2:. */
-
- BENTRY COM_ICNT <UNIT>
-
- MOV AX,UNIT ; Point to COM1: or COM2: save area.
- CALL SET_SI ;
-
- MOV AX,[SI].SIZE_RDATA ; Get number of bytes used.
-
- BEND COM_ICNT
-
- .SBHED <COM_GETC -- Get the Next Received Character>
-
- ; int /* Next character in input buffer or EOF. */
- ; com_getc(unit) /* Reads next character in input buffer. */
- ; int unit; /* 1 ==> COM1:, 2 ==> COM2:. */
- ;
- ; Returns the next character from the receive buffer and
- ; removes it from the buffer.
-
- BENTRY COM_GETC <UNIT>
-
- MOV AX,UNIT ; Point to COM1: or COM2: save area.
- CALL SET_SI ;
-
- CMP [SI].SIZE_RDATA,0 ; Is there anything in the buffer?
- JE L12 ; (nothing)
-
- MOV ES,[SI].RBUF_SEG ; Get receive buffer segment number.
- MOV DI,[SI].RBUF_OFF ; Get receive buffer offset.
- MOV BX,[SI].START_RDATA ; Fetch next data byte.
- MOV AL,ES:[BX+DI] ; Get data from buffer.
- XOR AH,AH
-
- INC BX ; Bump START_RDATA so it points at next char.
- CMP BX,[SI].RBUF_SIZE ; See if past end.
- JB L10 ; If not then skip.
- XOR BX,BX ; Adjust to beginning.
- L10: MOV [SI].START_RDATA,BX ; Save the new START_RDATA value.
-
- DEC [SI].SIZE_RDATA ; One less character.
- JMP SHORT L14 ; Skip to common return code.
-
- L12: MOV AX,-1 ; Indicate no characters available.
-
- L14: BEND COM_GETC
-
- .SBHED <COM_OCNT -- Returns Number of Free Bytes>
-
- ; int /* Number of free bytes in output buffer. */
- ; com_ocnt(unit) /* Returns number of free bytes in output buffer. */
- ; int unit; /* 1 ==> COM1:, 2 ==> COM2:. */
-
- BENTRY COM_OCNT <UNIT>
-
- MOV AX,UNIT ; Point to COM1: or COM2: save area.
- CALL SET_SI ;
-
- MOV AX,[SI].TBUF_SIZE ; Get the size of the x-mit buffer.
- SUB AX,[SI].SIZE_TDATA ; Subtract the number of bytes used.
-
- BEND COM_OCNT
-
- .SBHED <COM_PUTC -- Queue a Character for Output>
-
- ; bool /* Returns FALSE if no more room. */
- ; com_putc(unit, ch) /* Writes a character to the output buffer. */
- ; int unit; /* 1 ==> COM1:, 2 ==> COM2:. */
- ; char ch; /* The character to write. */
-
- ; Note that there is an implicit interlock with the interrupt
- ; level. It is OK for an interrupt to occur between incrementing
- ; SIZE_TDATA and the end of the code that monkeys with the interrupt
- ; enable bits. The worst that can happen is that there will be an
- ; extra interrupt, which will be ignored (because SIZE_TDATA will be
- ; zero again by then).
-
- BENTRY COM_PUTC <UNIT,OCHAR>
-
- MOV AX,UNIT ; Point to COM1: or COM2: save area.
- CALL SET_SI ;
-
- MOV AX,[SI].TBUF_SIZE ; Get the size of the x-mit buffer.
- SUB AX,[SI].SIZE_TDATA ; Subtract the number of bytes used.
- JE L24 ; No more free space.
-
- MOV ES,[SI].TBUF_SEG ; Get transmit buffer segment number.
- MOV DI,[SI].TBUF_OFF ; Get transmit buffer offset.
- MOV BX,[SI].END_TDATA ; BX points to free space.
- MOV AL,OCHAR ; Move data from stack to x-mit buffer.
- MOV ES:[BX+DI],AL
- INC BX ; Increment END_TDATA to point to free space.
- CMP BX,[SI].TBUF_SIZE ; See if past end.
- JB L20 ; If not then skip.
- XOR BX,BX ; Adjust to beginning.
- L20: MOV [SI].END_TDATA,BX ; Save new END_TDATA.
-
- ; (Implicit interlock with interrupt level):
- INC [SI].SIZE_TDATA ; One more character in x-mit buffer.
-
- MOV DX,[SI].COMX_BASE
- ADD DX,IER ; See if tx interrupts are enabled.
- IN AL,DX
- AND AL,TXINT
- OR AL,AL
- JNZ L22
- MOV AL,RXINT+TXINT ; If not then set them.
- OUT DX,AL
- L22: ; (End of implicit interlock)
-
- MOV AX,TRUE ; Indicate all's OK.
- JMP SHORT L26 ; Go join common return code.
-
- L24: MOV AX,FALSE ; No more space in buffer.
-
- L26: BEND COM_PUTC
-
- .SBHED <COM_LOOPC -- Write to the Input Buffer>
-
- ; bool /* Returns FALSE if no more room. */
- ; com_loopc(unit, ch) /* Writes a character to the input buffer. */
- ; int unit; /* 1 ==> COM1:, 2 ==> COM2:. */
- ; char ch; /* The character to write. */
-
- BENTRY COM_LOOPC <UNIT,OCHAR>
-
- MOV AX,UNIT ; Point to COM1: or COM2: save area.
- CALL SET_SI ;
-
- CLI ; ******* Disable Interrupts *******
- MOV DX,[SI].RBUF_SIZE ;;; Get the size of the receive buffer.
- CMP [SI].SIZE_RDATA,DX ;;; See if any room for more data.
- JAE L32 ;;; If no room then quit.
-
- MOV ES,[SI].RBUF_SEG ;;; Get receive buffer segment number.
- MOV DI,[SI].RBUF_OFF ;;; Get receive buffer offset.
- MOV BX,[SI].END_RDATA ;;; BX points to free space.
- MOV AL,OCHAR ;;; Get data.
- MOV ES:[BX+DI],AL ;;; Send data to buffer.
- INC [SI].SIZE_RDATA ;;; Got one more character.
- INC BX ;;; Increment END_RDATA pointer.
- CMP BX,DX ;;; See if gone past end.
- JL L30 ;;; If not then skip,
- XOR BX,BX ;;; else adjust to beginning.
- L30: MOV [SI].END_RDATA,BX ;;; Save value.
-
- STI ;;; ******* Enable Interrupts *******
- MOV AX,TRUE ;;; Indicate success.
- JMP SHORT L34 ; Go join common return code.
-
- L32: STI ;;; ******* Enable Interrupts *******
- MOV AX,FALSE ;;; Indicate no more room.
-
- L34: BEND COM_LOOPC
-
- .SBHED <COM_BON -- Turn On BREAK Condition>
-
- ; void
- ; com_bon(unit) /* Turns on BREAK. */
- ; int unit; /* 1 ==> COM1:, 2 ==> COM2:. */
- ;
- ; Causes the UART to send the BREAK condition.
-
- BENTRY COM_BON <UNIT>
-
- MOV AX,UNIT ; Point to COM1: or COM2: save area.
- CALL SET_SI ;
-
- MOV DX,[SI].COMX_BASE
- ADD DX,LCR
- MOV AL,BREAK ; Set break condition.
- OUT DX,AL
-
- BEND COM_BON
-
- .SBHED <COM_BOFF -- Turn Off BREAK Condition>
-
- ; void
- ; com_boff(unit) /* Turns off BREAK. */
- ; int unit; /* 1 ==> COM1:, 2 ==> COM2:. */
- ;
- ; Returns the transmit line to the normal state.
-
- BENTRY COM_BOFF <UNIT>
-
- MOV AX,UNIT ; Point to COM1: or COM2: save area.
- CALL SET_SI ;
-
- MOV DX,[SI].COMX_BASE
- ADD DX,LCR
- MOV AL,MODE ; Restore the line control register.
- OUT DX,AL
-
- BEND COM_BOFF
-
- .SBHED <COM_BREAK -- Complete BREAK Sequence>
-
- ; void
- ; com_break(unit) /* Sends complete BREAK sequence. */
- ; int unit; /* 1 ==> COM1:, 2 ==> COM2:. */
-
- BENTRY COM_BREA <UNIT>
-
- MOV AX,UNIT ; Point to COM1: or COM2: save area.
- CALL SET_SI ;
-
- MOV DX,[SI].COMX_BASE
- ADD DX,LCR
- MOV AL,BREAK ; Set break condition.
- OUT DX,AL
-
- MOV CX,0 ; Wait a while.
- WAIT: LOOP WAIT
-
- MOV AL,MODE ; Restore the line control register.
- OUT DX,AL
-
- BEND COM_BREA
-
- ENDPS
- END
-